home *** CD-ROM | disk | FTP | other *** search
- ;* BIGMATH.ASM
- ;************************************************************************
- ;* *
- ;* PC Scheme/Geneva 4.00 Borland TASM code *
- ;* *
- ;* (c) 1985-1988 by Texas Instruments, Inc. See COPYRIGHT.TXT *
- ;* (c) 1992 by L. Bartholdi & M. Vuilleumier, University of Geneva *
- ;* *
- ;*----------------------------------------------------------------------*
- ;* *
- ;* Bignum mathematical support *
- ;* *
- ;*----------------------------------------------------------------------*
- ;* *
- ;* Created by: John Jensen Date: 1985 *
- ;* Revision history: *
- ;* - 18 Jun 92: Renaissance (Borland Compilers, ...) *
- ;* *
- ;* ``In nomine omnipotentii dei'' *
- ;************************************************************************
- IDEAL
- %PAGESIZE 60, 132
- MODEL medium
- LOCALS @@
-
- INCLUDE "scheme.ash"
-
- CODESEG
-
- ;************************************************************************
- ;* Convert a bignum to a flonum *
- ;* Calling sequence: big2flo(bigptr,floptr) *
- ;* Where bigptr:pointer to bignum workspace *
- ;* floptr: pointer to flonum *
- ;************************************************************************
- P8087
- PROC C big2flo USES si di, @@bignum, @@flonum
- LOCAL @@temp:QWORD, @@exponent:WORD
- push ds ; assume es = ds
- pop es
- cld
- mov si, [@@bignum] ; Point ds:si to working bignum
- mov bx, [(BIGDATA si).len]
- lea si, [(BIGDATA si).lsw]
- cmp bx, 3
- ja @@atleast64bits
- mov cx, 4 ; to fill in gaps
- lea di, [@@temp]
- movsw ; get least sig. word in dx
- dec cx
- dec bx
- jz @@smalllong
- movsw ; get next least sig. word in di
- dec cx
- dec bx
- jz @@smalllong
- movsw ; Get 3rd least sig. word in bx
- dec cx
- @@smalllong:
- xor ax, ax
- rep stosw ; wipe out the rest
- fild [@@temp]
- jmp @@storeback
-
- @@atleast64bits:
- shl bx, 1 ; Point si to 4th most sig. word
- sub bx, TYPE QWORD ; now bx is the size of what we discarded
- add si, bx
- shl bx, 1 ; get lost size in bits
- shl bx, 1
- shl bx, 1
- test [BYTE si+(TYPE QWORD)-1], 80h ; is most significant bit set ?
- jz @@noadjust ; if so, shift in a couple a 0s
- add bx, 8 ; compensate for the 'filling' byte
- inc si
- lea di, [@@temp]
- mov cx, 7
- rep movsb
- mov [BYTE di], 0 ; clear most significant byte
- lea si, [@@temp]
- @@noadjust:
- mov [@@exponent], bx
- fild [@@exponent] ; load the exponent
- fild [QWORD si]
- fscale ; 'idiosyncracy'
- fstp st(1)
- @@storeback:
- mov si, [@@bignum]
- test [(BIGDATA si).sign], 1
- jz @@positive
- fchs
- @@positive:
- mov di, [@@flonum]
- fstp [QWORD di]
- xor ax, ax ; Return 0: all well
- ret
- ENDP big2flo
-
- ;************************************************************************
- ;* Convert fixnum to bignum *
- ;* Calling sequence: fix2big(fixnum,bigptr) *
- ;* Where fixnum:Integer of small absolute value *
- ;* bigptr: Pointer to bignum space *
- ;************************************************************************
- PROC C fix2big USES si di, @@fixnum, @@bignum
- mov di, [@@bignum]
- mov [(BIGDATA di).len], 1
- mov ax, [@@fixnum]
- xor bx, bx
- or ax, ax
- jns @@positive
- neg ax
- inc bx
- @@positive:
- mov [(BIGDATA di).lsw], ax
- mov [(BIGDATA di).sign], bl
- ret
- ENDP fix2big
-
- ;************************************************************************
- ;* Compare magnitudes of two bignums *
- ;* Calling sequence: data = magcomp(big1,big2) *
- ;* Where big1,big2:pointers to bignum buffers *
- ;* data: a positive integer as follows: *
- ;* Bit 0 set iff |BIG1| < |BIG2| *
- ;* Bit 1 set iff |BIG1| > |BIG2| *
- ;* Bit 2 set iff BIG1 < BIG2 *
- ;* Bit 3 set iff BIG1 > BIG2 *
- ;* Bit 4 set iff BIG1,BIG2 have same sign *
- ;************************************************************************
- PROC C magcomp USES si di, @@bignum1, @@bignum2
- push ds ; assume es = ds
- pop es
- xor al, al ; this is the result
- xor dx, dx
- mov si, [@@bignum1]
- mov di, [@@bignum2]
- mov ah, [(BIGDATA si).sign]
- mov dh, [(BIGDATA di).sign]
- xor dh, ah ; Put XOR of signs into carry
- shr dh, 1
- jc @@signskip
- or al, 10h
- @@signskip:
- rcl ah, 1
- mov cx, [(BIGDATA si).len]
- mov dx, [(BIGDATA di).len]
- cld
- cmpsw
- jb @@bigger2
- ja @@bigger1
- @@samelength:
- call msw1 ; If same size, point si,di to last words
- call msw2 ; (most significant)
- std
- repe cmpsw
- jb @@really2
- ja @@really1
- test ah, 1 ; Signs same?
- jz @@done
- @@differentsigns:
- test ah, 2 ; Is BIG1 positive?
- jnz @@greater2
- jz @@greater1
- @@bigger1:
- call msw1
- cmp [WORD si], 0 ; check high word
- jne @@really1
- mov si, [@@bignum1] ; restore si
- inc si
- inc si
- dec cx ; high order word is empty
- cmp cx, dx ; compare length's again
- je @@samelength
- jmp @@bigger1
-
- @@really1:
- or al, 2 ; Set the |BIG1|>|BIG2| bit
- test ah, 1 ; Signs same?
- jnz @@differentsigns
- test ah, 2 ; Both positive?
- jnz @@greater2
- @@greater1:
- or al, 8 ; Set the BIG1>BIG2 bit
- jmp @@done
-
- @@bigger2:
- push cx
- mov cx, dx ; swap cx and dx
- pop dx
- call msw2
- cmp [WORD di], 0 ; check high word
- jne @@really2
- mov di, [@@bignum2] ; restore di
- inc di
- inc di
- dec cx ; high order word is empty
- cmp dx, cx ; compare length's again
- je @@samelength
- jmp @@bigger2
-
- @@really2:
- or al, 1 ; Set the |BIG1|<|BIG2| bit
- test ah, 1 ; Signs same?
- jnz @@differentsigns
- test ah, 2 ; Both positive?
- jnz @@greater1
- @@greater2:
- or al, 4 ; Set the BIG1<BIG2 bit
- @@done:
- cld ; Set direction forward (JCJ-12/6/84)
- ret
-
- ; set up big1's index for comparison, used with magcomp
- PROC NOLANGUAGE msw1 NEAR
- shl cx, 1
- dec si
- add si, cx
- shr cx, 1
- ret
- ENDP msw1
-
- ; set up big2's index for comparison, used with magcomp
- PROC NOLANGUAGE msw2 NEAR
- shl cx, 1
- dec di
- add di, cx
- shr cx, 1
- ret
- ENDP msw2
- ENDP magcomp
-
- ;************************************************************************
- ;* Add magnitudes of bignums *
- ;* Calling sequence: bigadd(big1,big2) *
- ;* Where big1: bignum of lesser magnitude *
- ;* big2: bignum of greater magnitude *
- ;* When done, BIG2 will hold the sum *
- ;************************************************************************
- PROC C bigadd USES si di, @@bignum1, @@bignum2
- mov si, [@@bignum1]
- mov di, [@@bignum2]
- cld
- lodsw ; Get length of smaller bignum
- mov cx, ax ; Save length
- sub ax, [(BIGDATA di).len]
- neg ax
- push ax
- inc si ; Point si,di to bignums proper
- lea di, [(BIGDATA di).lsw]
- clc ; Prepare to add
- @@loop:
- lodsw
- adc [WORD di], ax ; Add to destination addend
- inc di ; use INC to preserve carry !
- inc di ; Point di to next word
- loop @@loop
- pop cx ; Fetch length difference (CF unchanged)
- jnc @@done
- mov si, [@@bignum2]
- jcxz @@samelength
- @@carryloop:
- inc [WORD di] ; Otherwise, add carry
- jnz @@done ; Jump if no resultant carry
- add di, 2 ; Point di to next word
- loop @@carryloop
- @@samelength:
- mov [WORD di], 1 ; Store last carry
- inc [(BIGDATA si).len]
- @@done:
- ret
- ENDP bigadd
-
- ;************************************************************************
- ;* Subtract magnitudes of bignums *
- ;* Calling sequence: bigsub(big1,big2) *
- ;* Where big1: bignum of lesser magnitude *
- ;* big2 ---- bignum of greater magnitude *
- ;* When done, BIG2 will hold the difference *
- ;************************************************************************
- PROC C bigsub USES si di, @@bignum1, @@bignum2
- push ds ; assume es = ds
- pop es
- mov si, [@@bignum1]
- mov di, [@@bignum2]
- cld
- lodsw ; Get length of smaller bignum
- mov cx, ax
- inc si ; Point si,di to bignums proper
- lea di, [(BIGDATA di).lsw]
- clc ; Prepare to subtract
- @@loop:
- lodsw
- sbb [WORD di], ax
- inc di ; use INC to preserve carry !
- inc di ; Point di to next word
- loop @@loop
- jnc @@pack
- @@borrowloop:
- mov ax, [WORD di] ; Fetch word
- sub ax, 1 ; Decrement and store
- stosw
- jc @@borrowloop
- @@pack:
- mov di, [@@bignum2]
- mov si, di ; Save pointer in si
- mov ax, [(BIGDATA si).len]
- mov cx, ax ; Save (length-1) in cx
- dec cx
- shl ax, 1 ; Point di to last word of bignum
- inc ax
- add di, ax
- std ; Direction backward
- xor ax, ax ; Find number of leading 0-words
- repz scasw ; (not counting least sig. word)
- jz @@smallskip
- inc cx ; at least 2 non-0 words
- @@smallskip:
- inc cx ; Form (length - # of leading 0-words)
- mov [(BIGDATA si).len], cx
- cld ; Clear the direction flag
- ret
- ENDP bigsub
-
- ;************************************************************************
- ;* Multiply two bignums *
- ;* Calling sequence: bigmul(big1,big2,big3) *
- ;* Where big1,big2:factors *
- ;* big3: destination of product *
- ;************************************************************************
- PROC C bigmul USES si di, @@bignum1, @@bignum2, @@result
- push ds ; assume es = ds
- pop es
- cld
- mov si, [@@bignum1]
- mov di, [@@bignum2]
- lodsw ; Fetch BIG1's length
- mov cx, ax ; Put sum of lengths in cx
- add cx, [(BIGDATA di).len]
- scasw ; Which has greater magnitude?
- jnb @@theyrokay
- xchg di, si
- @@theyrokay:
- lodsb ; Fetch one factor's sign
- xor al, [BYTE di] ; XOR with the other factor's sign
- inc di ; Point di to bignum proper
- mov bx, di
- mov di, [@@result] ; Store length into product
- xchg ax, cx
- stosw
- push ax ; Save total length of product
- xchg ax, cx ; Store sign byte into product
- stosb
- push di ; Set product to 0 over whole length
- xor ax, ax
- rep stosw
- pop di
- xchg di, bx ; Restore bx and di
- mov cx, [di-3] ; Fetch length of BIG2
- sub bx, si ; Point [bx+si-2] to product
- dec bx
- dec bx
- mov [@@bignum1], si
- @@outer:
- push cx ; Save counter of BIG2 words
- ; Add (BIG1*part of BIG2) to current product
- mov si, [@@bignum1]
- mov cx, [si-3] ; Get number of words in bignum
- push bp
- xor bp, bp ; our carry
- @@inner:
- lodsw ; Get factor part from BIG1
- mul [WORD di]
- add ax, bp
- adc dx, 0
- add [bx+si], ax ; Add product part into BIG3
- adc dx, 0 ; Adjust and store carry
- mov bp, dx
- loop @@inner ; Continue for all BIG1
- pop bp
- mov [bx+si+2], dx ; Store carry remaining
-
- pop cx ; Restore BIG2 counter
- inc di ; Point di to next word in BIG2
- inc di
- inc bx ; Point bx to next word in BIG3
- inc bx
- loop @@outer ; Continue for all BIG2
-
- mov bx, [@@result]
- pop si ; Point si to last word of product
- shl si, 1
- cmp [WORD si+bx+1], 0 ; Test last word for zero
- jnz @@done
- dec [(BIGDATA bx).len]
- @@done:
- ret
- ENDP bigmul
-
- ;************************************************************************
- ;* Divide one bignum by another *
- ;* Calling sequence: bigdiv(dvdnd,dvsr,quot) *
- ;* Where dvdnd: dividend *
- ;* dvsr: divisor *
- ;* quot: quotient *
- ;************************************************************************
- PROC C bigdiv USES si di, $$dividend, @@divisor, @@quotient
- LOCAL $$divisorend, $$align, @@bitcount, $$divisorsize
-
- push ds ; assume es = ds
- pop es
- mov di, [@@quotient] ; Get pointers to arguments
- mov si, [$$dividend]
- mov bx, [@@divisor]
- cld
- lodsw ; Get dividend length
- mov cx, [(BIGDATA bx).len]
- cmp cx, 1 ; Check divisor for 0
- jne @@longdiv
-
- mov dx, [(BIGDATA bx).lsw]
- or dx, dx
- jnz @@divisorok
- mov ax, 1
- jmp @@ret
- @@divisorok:
- mov cl, [(BIGDATA bx).sign]
- push ax ; save the dividend'd size
- mov bx, ax
- dec bx
- shl bx, 1
- cmp [((BIGDATA si+bx).lsw)-2], dx ; will result be smaller ?
- sbb ax, 0
- stosw ; write back the quotient's size
- lodsb ; get dividend's sign
- xor al, cl
- stosb
- add si, bx ; make si point to the divisor's end
- add di, bx ; and di to the quotient's end
- mov bx, dx ; bx is the divisor
- xor dx, dx ; clear the carry
- std ; start at most significant digit
- pop cx
- @@fastloop:
- lodsw
- div bx
- stosw
- loop @@fastloop
-
- mov [((BIGDATA si).len)-1], 1
- mov [((BIGDATA si).lsw)-1], dx ; store remainder
- jmp @@retok
-
- @@longdiv:
- inc bx ; my, that's ugly ! remember bx has been
- ; incremented... it shortens the code
- mov dx, cx ; Find & store pointer to last divisor word
- shl dx, 1
- add dx, bx
- mov [$$divisorend], dx
- sub ax, cx ; Find dividend-divisor length difference
- mov dx, ax ; Save in dx for now
- inc ax ; Store maximum quotient length (words)
- stosw
- inc cx ; Save length of working divisor (overwrite size!)
- mov [$$divisorsize], cx
- dec ax ; Find and store quotient bit count
- shl ax, 1
- shl ax, 1
- shl ax, 1
- shl ax, 1
- inc ax
- mov [@@bitcount], ax
- lodsb ; Get dividend sign
- xor al, [((BIGDATA bx).sign)-1]
- stosb
- mov [$$dividend], si ; save proper pointers
- mov [@@quotient], di
- xor ax, ax ; Zero first two words of quotient
- stosw
- std
- stosw
- dec dx ; Account for extra divisor word
- shl dx, 1 ; Store divisor-dividend alignment
- add dx, si
- mov [$$align], dx
- mov [WORD bx], 0 ; Put 0-word at start of divisor
- mov [@@divisor], bx ; Save pointer to working divisor
- @@findwork:
- call divcmp ; Dividend less than aligned divisor?
- jb @@dividebit0
- test [WORD bx], 8000h ; Can divisor be shifted left?
- jnz @@dividebit1
- mov si, [@@divisor] ; Otherwise, shift entire divisor left
- mov cx, [$$divisorsize]
- clc ; Start by shifting in 0
- @@shiftleft:
- rcl [WORD si], 1 ; Shift through divisor word
- inc si ; Point si to next word
- inc si ; (preserving carry)
- loop @@shiftleft
- inc [@@bitcount]
- jmp @@findwork ;See if divisor is big enough yet
-
- @@divide:
- call divcmp ; Dividend less than aligned divisor?
- cld ; (Direction forward)
- jb @@dividebit0
- mov si, [$$align] ; Otherwise, subtract divisor
- mov di, si
- mov bx, [@@divisor]
- sub bx, si
- dec bx
- dec bx
- mov cx, [$$divisorsize]
- clc ; No carry in
- @@inner:
- lodsw
- sbb ax, [si+bx]
- stosw
- loop @@inner
- @@dividebit1:
- clc ; Clear carry (to rotate 1 in)
- @@dividebit0:
- cmc
- mov si, [@@quotient] ; Fetch pointer to quotient
- mov cx, [si-3] ; Fetch quotient length
- @@quotientloop:
- rcl [WORD si], 1 ; Rotate bit in
- inc si ; preserving carry
- inc si
- loop @@quotientloop
- dec [@@bitcount]
- jz @@done
- mov si, [$$divisorend] ; realign divisor (shr)
- mov cx, [$$divisorsize]
- std
- cmp [WORD si], 0 ; Time to shift divisor words?
- jnz @@skipwordshift
- mov bx, si ; Save last word pointer
- mov dx, cx ; Save word count
- mov di, si ; Destination = source+2
- dec si
- dec si
- dec cx ; Shift significant divisor words
- rep movsw
- xor ax, ax ; Clear least significant word
- stosw
- mov si, bx ; Restore last word pointer
- mov cx, dx ; Restore count
- sub [$$align], 2 ; Reset divisor alignment
- @@skipwordshift:
- clc ; Shift 0 in
- @@shiftright:
- rcr [WORD si], 1
- dec si
- dec si
- loop @@shiftright
- jmp @@divide
-
- @@done:
- mov bx, [$$dividend] ; Fetch dividend pointer
- mov di, [bx-3] ; Fetch former length of dividend
- dec di ; Put length-1 in cx
- mov cx, di
- shl di, 1 ; Point di to last dividend word
- add di, bx
- std
- xor ax, ax ; Pack as in BIGSUB
- repe scasw
- jz @@skipsmall
- inc cx
- @@skipsmall:
- inc cx
- mov [bx-3], cx ; Save in bignum size field
- mov bx, [@@quotient] ; Fetch quotient pointer
- mov di, [bx-3] ; Point bx+di to last quotient word
- shl di, 1
- cmp [WORD bx+di-2], 0 ; If last word is 0, decrease length
- jnz @@retok
- dec [WORD bx-3]
- @@retok:
- xor ax, ax ; success
- @@ret:
- cld
- ret
-
- ; Compare working divisor to dividend
- PROC NOLANGUAGE divcmp NEAR
- mov di, [$$divisorend] ; Get pointer to last divisor word
- mov cx, [$$divisorsize] ; Fetch number of compares to do
- mov si, [$$align] ; Get dividend pointer
- mov ax, cx
- cmp si, [$$dividend] ; Dividend longer than divisor?
- jae @@skipadjust
- dec cx ; Don't compare first divisor word
- @@skipadjust:
- dec ax ; Adjust pointer into dividend
- shl ax, 1
- add si, ax
- mov bx, di ; Save pointer to last divisor byte
- std
- repe cmpsw
- ret
- ENDP divcmp
-
- ENDP bigdiv
-
- END
-